home *** CD-ROM | disk | FTP | other *** search
- include lmacros.h
-
- assume ds:dataseg
- public Sssave,Spsave,Intstk_,doret,Isat_,dbase_,cbase_
- extrn _Dorg_:byte,_Corg_:byte
-
- ifdef FARPROC
- extrn ctick_:far
- else
- extrn ctick_:near
- endif
-
- dbase dw seg _Dorg_ ; save loc for ds (must be in code segment)
-
- ; common routine for interrupt return
-
- ifdef FARPROC
- doret proc far
- else
- doret proc near
- endif
- cmp Isat_,1
- jnz notat ; Only one 8259, so skip this stuff
- mov al,0bh ; read in-service register from
- out 0a0h,al ; secondary 8259
- nop ; settling delay
- nop
- nop
- in al,0a0h ; get it
- or al,al ; Any bits set?
- jz notat ; nope, not a secondary interrupt
- mov al,20h ; Get EOI instruction
- out 0a0h,al ; Secondary 8259 (PC/AT only)
- notat: mov al,20h ; 8259 end-of-interrupt command
- out 20h,al ; Primary 8259
- pop es
- pop di
- pop si
- pop bp
- pop dx
- pop cx
- pop bx
- pop ax
- mov ss,Sssave
- mov sp,Spsave ; restore original stack context
- pop ds
- iret
- doret endp
-
- ; Null interrupt handler
- procdef nullvec
- iret
- pend nullvec
-
- ; setvect - set interrupt vector
- ; called from C as follows
- ; setvect(vec,vecval)
- ; char vec; /* Interrupt number */
- ; void (*vecval)(); /* offset (and segment in large code model) */
-
- procdef setvect,<<vec,byte>,<ipval,fptr>>
- mov dx,word ptr ipval
- push ds ; save
- ifdef FARPROC
- mov ds,word ptr ipval+2
- else
- mov ax,cs
- mov ds,ax
- endif
- mov ah,25h
- mov al,vec
- int 21h
- pop ds ; restore
- pret
- pend setvect
-
- ; getvect - return current interrupt vector
- ; called from C as
- ; long /* Returns CS in high word, IP in low word */
- ; getvect(vecnum)
- ; char vecnum; /* Interrupt number */
-
- procdef getvect,<<vecnum,byte>>
- mov ah,35h
- mov al,vecnum
- push es ; save, since DOS uses it for a return value
- int 21h
- mov dx,es ; CS value into DX (C high word)
- mov ax,bx ; IP value into AX (C low word)
- pop es ; restore es
- pret
- pend getvect
-
- ; kbraw - raw, nonblocking read from console
- ; If character is ready, return it; if not, return -1
-
- procdef kbraw
- mov ah,06h ; Direct Console I/O
- mov dl,0ffh ; Read from keyboard
- int 21h ; Call DOS
- jz nochar ; zero flag set -> no character ready
- mov ah,0 ; valid char is 0-255
- pret
- nochar:
- mov ax,-1 ; no char, return -1
- pret
- pend kbraw
-
- ; Return nonzero if a key is ready, without reading it
- procdef kbhit
- mov ah,0bh ; Check Standard Input Status
- int 21h ; Call DOS
- mov ah,0 ; clear upper half of return value
- pret
- pend kbhit
-
- ; istate - return current interrupt state
- procdef istate
- pushf
- pop ax
- and ax,200h
- jnz ion1
- pret
- ion1: mov ax,1
- pret
- pend istate
-
- ; dirps - disable interrupts and return previous state: 0 = disabled,
- ; 1 = enabled
-
- procdef dirps
- pushf ; save state on stack
- cli ; interrupts off
- pop ax ; original flags -> ax
- and ax,200h ; 1<<9 is IF bit
- jnz ion ; nonzero -> interrupts were on
- pret
- ion: mov ax,1
- pret
- pend dirps
-
- ; restore - restore interrupt state: 0 = off, nonzero = on
-
- procdef restore,<<istate,byte>>
- test istate,0ffh
- jz ioff
- sti
- pret
- ioff: cli
- pret
- pend restore
-
- ; enable - enable interrupts unconditionally
- procdef enable
- sti
- pret
- pend enable
-
- ; Halt until an interrupt occurs, then return
- procdef eihalt
- sti ; make sure interrupts are enabled
- hlt
- pret
- pend eihalt
-
- ; multitasker types
- NONE equ 0
- DOUBLEDOS equ 1
- DESQVIEW equ 2
-
- ; Relinquish processor so other task can run
- procdef giveup
- pushf ;save caller's interrupt state
- sti ;re-enable interrupts
- cmp mtasker,DOUBLEDOS
- jnz givedesqview
- mov al,2 ; 110 ms
- mov ah,0eeh
- int 21h
- popf ; restore interrupts
- pret
- givedesqview:
- cmp mtasker,DESQVIEW
- jnz notask
- mov ax, 1000h
- int 15h
- popf ; restore interrupts
- pret
- notask:
- hlt ; wait for an interrupt
- popf ; restore interrupts
- pret
- pend giveup
-
- ; check for a multitasker running
- procdef chktasker
- mov mtasker, NONE
- ; do the doubledos test
- mov ah, 0e4h
- int 21h
- cmp al, 1
- jz isdos
- cmp al, 2
- jnz test_desq
- isdos: mov mtasker, DOUBLEDOS
- pret
-
- ; test for desqview
- test_desq:
- mov ax, 2b01h
- mov cx, 4445h
- mov dx, 5351h
- int 21h
- cmp al, 0ffh
- jnz isdesq
- pret
- isdesq: mov mtasker, DESQVIEW
- pret
- pend chktasker
-
- ; getss - Read SS for debugging purposes
- procdef getss
- mov ax,ss
- pret
- pend getss
-
- ; Internet checksum subroutine
- ; Compute 1's-complement sum of data buffer
- ; Uses an unwound loop inspired by "Duff's Device" for performance
- ;
- ; Called from C as
- ; unsigned short
- ; lcsum(buf,cnt)
- ; unsigned short *buf;
- ; unsigned short cnt;
- procdef lcsum,<<buf,ptr>,<cnt,word>>
- pushds ; save if using large model
- push si
- ldptr si,buf,ds ; ds:si = buf
- mov cx,cnt ; cx = cnt
- cld ; autoincrement si
-
- mov ax,cx
- shr cx,1 ; cx /= 16, number of loop iterations
- shr cx,1
- shr cx,1
- shr cx,1
-
- inc cx ; make fencepost adjustment for 1st pass
- and ax,15 ; ax = number of words modulo 16
- shl ax,1 ; *=2 for word table index
- lea bx,jtable ; bx -> branch table
- add bx,ax ; index into jump table
- clc ; initialize carry = 0
- mov dx,0 ; clear accumulated sum
- jmp word ptr[bx] ; jump into loop
-
- ; Here the real work gets done. The numeric labels on the lodsw instructions
- ; are the targets for the indirect jump we just made.
- ;
- ; Each label corresponds to a possible remainder of (count / 16), while
- ; the number of times around the loop is determined by the quotient.
- ;
- ; The loop iteration count in cx has been incremented by one to adjust for
- ; the first pass.
- ;
- deloop: lodsw
- adc dx,ax
- l15: lodsw
- adc dx,ax
- l14: lodsw
- adc dx,ax
- l13: lodsw
- adc dx,ax
- l12: lodsw
- adc dx,ax
- l11: lodsw
- adc dx,ax
- l10: lodsw
- adc dx,ax
- l9: lodsw
- adc dx,ax
- l8: lodsw
- adc dx,ax
- l7: lodsw
- adc dx,ax
- l6: lodsw
- adc dx,ax
- l5: lodsw
- adc dx,ax
- l4: lodsw
- adc dx,ax
- l3: lodsw
- adc dx,ax
- l2: lodsw
- adc dx,ax
- l1: lodsw
- adc dx,ax
- l0: loop deloop ; :-)
-
- adc dx,0 ; get last carries
- adc dx,0
- mov ax,dx ; result into ax
- xchg al,ah ; byte swap result (8088 is little-endian)
- pop si
- popds ; all done
- pret
- pend lcsum
-
- ; Clock tick interrupt handler
- public btick_
- btick_ proc far
- ; Note that we don't save DS. It has already been saved by the BIOS,
- ; and if we saved and restored it the indirect jmp at the end would
- ; go off into the ozone.
- mov ds,cs:dbase ; establish interrupt data segment
-
- mov Sssave,ss ; stash user stack context
- mov Spsave,sp
-
- mov ss,cs:dbase
- lea sp,Intstk_+512
-
- push ax ; save user regs on interrupt stack
- push bx
- push cx
- push dx
- push bp
- push si
- push di
- push es
- mov ax,ds
- mov es,ax
-
- call ctick_
-
- pop es
- pop di
- pop si
- pop bp
- pop dx
- pop cx
- pop bx
- pop ax
- mov ss,Sssave
- mov sp,Spsave ; restore original stack context
- jmp dword ptr Tvec_ ; link to previous vector
- btick_ endp
-
- ; Convert 32-bit int in network order to host order (dh, dl, ah, al)
- procdef get32,<<cp32,ptr>>
- pushds
- cld
- push si
- ldptr si,cp32,ds
- lodsw
- mov dh,al ; high word to dx, a-swapping as we go
- mov dl,ah
- lodsw
- xchg al,ah ; low word stays in ax, just swap
- pop si
- popds
- pret
- pend get32
-
- ; Convert 16-bit int in network order to host order (ah, al)
- procdef get16,<<cp16,ptr>>
- pushds
- cld
- push si
- ldptr si,cp16,ds
- lodsw
- xchg al,ah ; low word stays in ax, just swap
- pop si
- popds
- pret
- pend get16
-
- ; Convert 32-bit int to network order, returning new pointer
- procdef put32,<<cpo32,ptr>,<pi32,dword>>
- pushds
- push es
- cld
- push di
- push si
- ldptr di,cpo32,es ; point di to network output buffer
- lea si,pi32 ; point si to input doubleword
- ifdef LONGPTR
- mov ax,ss
- mov ds,ax
- endif
- lodsw ; fetch low word of machine version
- mov dh,al ; swap bytes and save
- mov dl,ah
- lodsw ; fetch high word
- xchg ah,al ; byte swap
- stosw ; store in output
- mov ax,dx ; retrieve low word and store in output
- stosw
- mov ax,di ; return incremented output pointer
- pop si
- pop di
- pop es
- popds
- pret
- pend put32
-
- ; Convert 16-bit int to network order, returning new pointer
- procdef put16,<<cpo16,ptr>,<pi16,word>>
- push es
- cld
- push di
- ldptr di,cpo16,es
- mov ax,pi16 ; fetch source word in machine order
- xchg ah,al ; swap bytes
- stosw ; save in network order
- mov ax,di ; return new output pointer to user
- pop di
- pop es
- pret
- pend put16
-
- finish
-
- public Tvec_
-
- dataseg segment para public 'data'
- jtable dw l0,l1,l2,l3,l4,l5,l6,l7,l8,l9,l10,l11,l12,l13,l14,l15
- dbase_ dw seg _Dorg_
- cbase_ dw seg _Corg_
- bss Spsave:word,2
- bss Sssave:word,2
- bss Intstk_:byte,512
- bss mtasker:byte,1
- bss Tvec_:word,4
- dataseg ends
- end
-